home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / gnu_st.lha / gnu_st / smalltalk-1.1.1 / Behavior.st < prev    next >
Text File  |  1991-09-12  |  11KB  |  464 lines

  1. "======================================================================
  2. |
  3. |   Behavior Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1990, 1991 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbb         12 Sep 91      Fixed isBytes and isWords so that subclassing for
  34. |              things like Dictionary works properly.
  35. |
  36. | sbyrne     25 Apr 89      created.
  37. |
  38. "
  39.  
  40. Object subclass: #Behavior
  41.        instanceVariableNames: 'superClass subClasses 
  42.                                methodDictionary instanceSpec'
  43.        classVariableNames: ''
  44.        poolDictionaries: ''
  45.        category: nil.
  46.  
  47. Behavior comment: 
  48. 'I am the parent class of all "class" type methods.  My instances know
  49. about the subclass/superclass relationships between classes, contain
  50. the description that instances are created from, and hold the method
  51. dictionary that''s associated with each class.  I provide methods for
  52. compiling methods, modifying the class inheritance hierarchy, examining the
  53. method dictionary, and iterating over the class hierarchy.' !
  54.  
  55. CFunctionDescs at: #CFunctionGensym put: 1!
  56.  
  57. !Behavior class methodsFor: 'C interface'!
  58.  
  59. defineCFunc: cFuncNameString
  60.   withSelectorArgs: selectorAndArgs
  61.   forClass: aClass 
  62.   returning: returnTypeSymbol 
  63.   args: argsArray
  64.     | stream gensym descriptor |
  65.     "This is pretty complex.  What I want to provide is a very efficient way
  66.      of calling a C function.  I create a descriptor object that holds the
  67.      relevant information regarding the C function.  I then compile the
  68.      method that's to be invoked to call the C function.  This method uses the
  69.      primitive #255 to perform the actual call-out.  To let the primitive
  70.      know which descriptor to use, I arrange for the first and only method
  71.      literal of the compiled method to be an association that contains as
  72.      its value the C function descriptor object.  I add new associations to
  73.      the global shared pool 'CFunctionDescs', and reference the newly
  74.      generated key in the text of the compiled method."
  75.     gensym _ Symbol intern: ('CFunction' , CFunctionGensym printString).
  76.     CFunctionGensym _ CFunctionGensym + 1.
  77.     descriptor _ self makeDescriptorFor: cFuncNameString
  78.                       returning: returnTypeSymbol
  79.                   withArgs: argsArray.
  80.     CFunctionDescs at: gensym put: descriptor.
  81.     stream _ WriteStream on: (String new: 5).
  82.     stream nextPutAll: selectorAndArgs.    
  83.     stream nextPutAll:
  84. '
  85.     <primitive: 255>
  86.     ^'.
  87.     gensym printOn: stream.
  88.     aClass compile: stream contents
  89. !!
  90.  
  91.  
  92.  
  93. !Behavior methodsFor: 'creating method dictionary'!
  94.  
  95. methodDictionary: aDictionary
  96.     methodDictionary _ aDictionary
  97. !
  98.  
  99. addSelector: selector withMethod: compiledMethod
  100.     methodDictionary at: selector put: compiledMethod
  101. !
  102.  
  103. removeSelector: selector
  104.     methodDictionary removeKey: selector
  105. !
  106.  
  107. compile: code
  108.     (code isKindOf: PositionableStream)
  109.         ifTrue: [ code _ code contents ].
  110.     (code isMemberOf: String)
  111.         ifFalse: [ code _ code asString ].
  112.     self compileString: code
  113. !
  114.  
  115. compile: code notifying: requestor
  116.     self notYetImplemented
  117. !
  118.  
  119. recompile: selector
  120.     self compile: (self sourceCodeAt: selector)
  121. !
  122.  
  123. decompile: selector
  124.     | method source |
  125.     method _ self compiledMethodAt: selector.
  126.     source _ method methodSourceString.
  127.     source isNil
  128.         ifTrue: [ ^self error: 'decompiler can''t decompile methods without source (yet)' ]
  129.     ifFalse: [ ^source ]
  130. !
  131.  
  132. edit: selector
  133.     | method sourceFile sourcePos |
  134.     method _ self compiledMethodAt: selector.
  135.     sourceFile _ method methodSourceFile.
  136.     sourceFile isNil
  137.         ifTrue: [ ^self error: 'decompiler can''t decompile methods without source (yet)' ].
  138.     sourcePos _ method methodSourcePos.
  139.     Smalltalk system: 'emacs -l st -smalltalk ', sourceFile, ' ', sourcePos printString
  140. !
  141.  
  142. compileAll
  143.     methodDictionary keysDo: [ :selector | self recompile: selector ]
  144. !
  145.  
  146. compileAllSubclasses
  147.     self allSubclassesDo: [ :subclass | subclass compileAll ]
  148. !!
  149.  
  150.  
  151.  
  152. !Behavior methodsFor: 'creating a class hierarchy'!
  153.  
  154. superclass: aClass
  155.     superClass _ aClass
  156. !
  157.  
  158. addSubclass: aClass
  159.     subClasses isNil ifTrue: [ subClasses _ Array new: 0 ].
  160.     subClasses _ subClasses copyWithout: aClass. "remove old class if any"
  161.     subClasses _ subClasses copyWith: aClass
  162. !
  163.  
  164. removeSubclass: aClass
  165.     subClasses _ subClasses copyWithout: aClass
  166. !!
  167.  
  168.  
  169.  
  170. !Behavior methodsFor: 'accessing the methodDictionary'!
  171.  
  172. selectors
  173.     methodDictionary isNil
  174.         ifTrue: [ ^Set new ]
  175.     ifFalse: [ ^methodDictionary keys ]
  176. !
  177.  
  178. allSelectors
  179.     | aSet |
  180.     aSet _ self selectors.
  181.     self allSuperclassesDo:
  182.         [ :superclass | aSet addAll: superclass selectors ].
  183.     ^aSet
  184. !
  185.  
  186. compiledMethodAt: selector
  187.     "Return the compiled method associated with selector, from the local
  188.     method dictionary.  Error if not found."
  189.     ^methodDictionary at: selector
  190. !
  191.  
  192. sourceCodeAt: selector
  193.     | method |
  194.     method _ self compiledMethodAt: selector.
  195.     ^method methodSourceString
  196. !
  197.  
  198. sourceMethodAt: selector
  199.     "This is too dependent on the original implementation"
  200.     self shouldNotImplement
  201. !!
  202.  
  203.  
  204.  
  205. !Behavior methodsFor: 'accessing instances and variables'!
  206.  
  207. allInstances
  208.     "Returns a set of all instances of the receiver"
  209.     | aSet |
  210.     aSet _ Set new.
  211.     self allInstancesDo: [ :anInstance | aSet add: anInstance ].
  212.     ^aSet
  213. !
  214.  
  215. instanceCount
  216.     | count anInstance |
  217.     count _ 0.
  218.     anInstance _ self someInstance.
  219.     [ anInstance notNil ]
  220.         whileTrue: [ count _ count + 1.
  221.                  anInstance _ anInstance nextInstance ].    
  222.     ^count
  223. !
  224.     
  225. instVarNames
  226.     self subclassResponsibility "### is this right?  Why is it here instead of
  227.                                  in ClassDescription?"
  228. !
  229.  
  230. subclassInstVarNames
  231.     self subclassResponsibility
  232. !
  233.  
  234. allInstVarNames
  235.     self subclassResponsibility
  236. !
  237.  
  238. classVarNames
  239.     self subclassResponsibility 
  240. !
  241.  
  242. allClassVarNames
  243.     self subclassResponsibility
  244. !
  245.  
  246. sharedPools
  247.     self subclassResponsibility
  248. !
  249.  
  250. allSharedPools
  251.     self subclassResponsibility
  252. !!
  253.  
  254.  
  255.  
  256. !Behavior methodsFor: 'accessing class hierarchy'!
  257.  
  258. subclasses
  259.     subClasses isNil
  260.     ifTrue: [ ^Set new ]
  261.     ifFalse: [ ^subClasses asSet ]
  262. !
  263.  
  264. allSubclasses
  265.     | aSet |
  266.     aSet _ Set new.
  267.     self allSubclassesDo: [ :subclass | aSet addAll: subclass subclasses ].
  268.     ^aSet
  269. !
  270.  
  271. withAllSubclasses
  272.     | aSet |
  273.     aSet _ Set with: self.
  274.     self allSubclassesDo: 
  275.         [ :subclass | aSet addAll: (subclass withAllSubclasses)    ].
  276.     ^aSet
  277. !
  278.  
  279. superclass
  280.     ^superClass
  281. !
  282.  
  283. allSuperclasses
  284.     | supers |
  285.     supers _ OrderedCollection new.
  286.     self allSuperclassesDo:
  287.         [ :superclass | supers addLast: superclass ].
  288.     ^supers
  289. !!
  290.  
  291.  
  292.  
  293. !Behavior methodsFor: 'testing the method dictionary'!
  294.  
  295. hasMethods
  296.     ^methodDictionary notNil and: [ methodDictionary size ~= 0 ]
  297. !
  298.  
  299. includesSelector: selector
  300.     "Returns true if the local method dictionary"
  301.     ^methodDictionary notNil and: [ methodDictionary includesKey: selector ]
  302. !
  303.  
  304. canUnderstand: selector
  305.     (self includesSelector: selector)
  306.         ifTrue: [ ^true ].
  307.     self allSuperclassesDo:
  308.         [ :superclass | (superclass includesSelector: selector)
  309.                         ifTrue: [ ^true ] ].
  310.     ^false
  311. !
  312.  
  313. whichClassIncludesSelector: selector
  314.     self allSuperclassesDo:
  315.         [ :superclass | (superclass includesSelector: selector)
  316.                         ifTrue: [ ^superclass ] ].
  317.     ^nil
  318. !
  319.  
  320. whichSelectorsAccess: instVarName
  321.     self notYetImplemented
  322. !
  323.  
  324. whichSelectorsReferTo: anObject
  325.     self notYetImplemented
  326. !
  327.  
  328. scopeHas: name ifTrue: aBlock
  329.     self notYetImplemented
  330. !!
  331.  
  332.  
  333.  
  334. !Behavior methodsFor: 'testing the form of the instances'!
  335.  
  336. isPointers
  337.     "Due to our representation bit 30 is inverted, so we invert the sense
  338.     of this test, and things work out fine."
  339.     ^(self instanceSpec bitAt: 30) = 0
  340. !
  341.  
  342. isBits
  343.     ^self isPointers not
  344. !
  345.  
  346. isBytes
  347.     ^self isPointers not & self isWords not
  348. !
  349.  
  350. isWords
  351.     ^self isPointers not & ((self instanceSpec bitAt: 29) ~= 0)
  352. !
  353.  
  354. isFixed
  355.     ^self isVariable not
  356. !
  357.  
  358. isVariable
  359.     ^(self instanceSpec bitAt: 28) ~= 0
  360. !
  361.  
  362. instSize
  363.     ^self instanceSpec bitAnd: 16r0FFFFFFF
  364. !!
  365.  
  366.  
  367.  
  368. !Behavior methodsFor: 'testing the class hierarchy'!
  369.  
  370. inheritsFrom: aClass
  371.     "Returns true if aClass is a superclass of the receiver"
  372.     | sc |
  373.     sc _ self.
  374.     [ sc _ sc superclass.
  375.       sc isNil ]
  376.         whileFalse:
  377.         [ sc == aClass ifTrue: [ ^true ] ].
  378.     ^false
  379. !
  380.  
  381. kindOfSubclass
  382.     self isVariable
  383.         ifTrue: [ self isBytes ifTrue: [ ^'variableByteSubclass: ' ].
  384.               self isPointers
  385.             ifTrue: [ ^'variableSubclass: ' ]
  386.             ifFalse: [ ^'variableWordSubclass: ' ] ]
  387.     ifFalse: [ ^'subclass: ' ]
  388. !!
  389.  
  390.  
  391.  
  392. !Behavior methodsFor: 'enumerating'!
  393.  
  394. allSubclassesDo: aBlock
  395.     "### I hope this means all direct subclasses"
  396.     subClasses notNil
  397.     ifTrue: [ subClasses do: [ :subclass | aBlock value: subclass ] ]
  398. !
  399.  
  400. allSuperclassesDo: aBlock
  401.     | class superclass |
  402.     class _ self.
  403.     [ superclass _ class superclass.
  404.       class _ superclass.
  405.       superclass notNil ] whileTrue:
  406.           [ aBlock value: superclass ]
  407. !
  408.  
  409. allInstancesDo: aBlock
  410.     | anInstance |
  411.     anInstance _ self someInstance.
  412.     [ anInstance notNil ]
  413.         whileTrue: [ aBlock value: anInstance.
  414.                  anInstance _ anInstance nextInstance ]
  415. !
  416.  
  417. allSubinstancesDo: aBlock
  418.     self allSubclassesDo:
  419.         [ :subclass | subclass allInstancesDo: aBlock ]
  420. !
  421.  
  422. selectSubclasses: aBlock
  423.     | aSet |
  424.     aSet _ Set new.
  425.     self allSubclassesDo: [ :subclass | (aBlock value: subclass)
  426.                                             ifTrue: [ aSet add: subclass ] ].
  427.     ^aSet
  428. !
  429.  
  430. selectSuperclasses: aBlock
  431.     | aSet |
  432.     aSet _ Set new.
  433.     self allSuperclassesDo: [ :superclass | (aBlock value: superclass)
  434.                                             ifTrue: [ aSet add: superclass ] ].
  435.     ^aSet
  436. !!
  437.  
  438.  
  439.  
  440.  
  441. !Behavior methodsFor: 'private'!
  442.  
  443. instanceSpec
  444.     ^instanceSpec
  445. !
  446.  
  447. setInstanceSpec: variableBoolean
  448.   words: wordsBoolean
  449.   pointers: pointersBoolean
  450.   instVars: anIntegerSize
  451.     instanceSpec _ 0.
  452.     "Due to our representation bit 30 is inverted, so we invert the sense
  453.     of this test, and things work out fine."
  454.     pointersBoolean
  455.         ifFalse: [ instanceSpec _ instanceSpec bitOr: ( 1 bitShift: 30 ) ].
  456.     wordsBoolean
  457.         ifTrue: [ instanceSpec _ instanceSpec bitOr: ( 1 bitShift: 29 ) ].
  458.     variableBoolean
  459.         ifTrue: [ instanceSpec _ instanceSpec bitOr: ( 1 bitShift: 28 ) ].
  460.     instanceSpec _ instanceSpec bitOr: (anIntegerSize bitAnd: 16r0FFFFFFF).
  461. !!
  462.